home *** CD-ROM | disk | FTP | other *** search
/ Planet Source Code Jumbo …e CD Visual Basic 1 to 7 / 5_2007-2008.ISO / data / Zips / Show_PNG_f2060184142007.psc / Simple PNG Example with RES / LoadPNG.cls < prev   
Text File  |  2007-04-12  |  47KB  |  1,625 lines

  1. VERSION 1.0 CLASS
  2. BEGIN
  3.   MultiUse = -1  'True
  4.   Persistable = 0  'NotPersistable
  5.   DataBindingBehavior = 0  'vbNone
  6.   DataSourceBehavior  = 0  'vbNone
  7.   MTSTransactionMode  = 0  'NotAnMTSObject
  8. END
  9. Attribute VB_Name = "LoadPNG"
  10. Attribute VB_GlobalNameSpace = False
  11. Attribute VB_Creatable = True
  12. Attribute VB_PredeclaredId = False
  13. Attribute VB_Exposed = False
  14. Option Explicit
  15. Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal length As Long)
  16. Private Declare Function SetDIBitsToDevice Lib "gdi32" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal dx As Long, ByVal dy As Long, ByVal SrcX As Long, ByVal SrcY As Long, ByVal Scan As Long, ByVal NumScans As Long, Bits As Any, BitsInfo As Any, ByVal wUsage As Long) As Long
  17. Private Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal XSrc As Long, ByVal YSrc As Long, ByVal dwRop As Long) As Long
  18. Private Declare Function GetDIBits Lib "gdi32" (ByVal aHDC As Long, ByVal hBitmap As Long, ByVal nStartScan As Long, ByVal nNumScans As Long, lpBits As Any, lpBI As Any, ByVal wUsage As Long) As Long
  19. Private Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long) As Long
  20. Private Declare Function CreateCompatibleBitmap Lib "gdi32" (ByVal hdc As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
  21. Private Declare Function SelectObject Lib "gdi32" (ByVal hdc As Long, ByVal hObject As Long) As Long
  22. Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
  23. Private Declare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As Long
  24. Private Declare Sub FillMemory Lib "kernel32.dll" Alias "RtlFillMemory" (Destination As Any, ByVal length As Long, ByVal Fill As Byte)
  25. Private Type BITMAPINFOHEADER
  26.  Size As Long
  27.  Width As Long
  28.  Height As Long
  29.  Planes As Integer
  30.  BitCount As Integer
  31.  Compression As Long
  32.  SizeImage As Long
  33.  XPelsPerMeter As Long
  34.  YPelsPerMeter As Long
  35.  ClrUsed As Long
  36.  ClrImportant As Long
  37. End Type
  38. Private RBD As Long
  39. Private IDATData() As Byte
  40. Dim IdataLen As Long
  41. Private Type IHDR
  42.  Width As Long
  43.  Height As Long
  44.  BitDepth As Byte
  45.  ColorType As Byte
  46.  Compression As Byte
  47.  Filter As Byte
  48.  Interlacing As Byte
  49. End Type
  50. 'For Decompression:
  51. Private Type CodesType
  52.  Lenght() As Long
  53.  code() As Long
  54. End Type
  55. Private m_Backcolor As Long
  56. Private Palettenbyte() As Byte
  57. Private OutStream() As Byte
  58. Private OutPos As Long
  59. Private InStream() As Byte
  60. Private Inpos As Long
  61. Private ByteBuff As Long
  62. Private BitNum As Long
  63. Private BitMask(16) As Long
  64. Private Pow2(16) As Long
  65. Private LC As CodesType
  66. Private dc As CodesType
  67. Private LitLen As CodesType
  68. Private Dist As CodesType
  69. Private TempLit As CodesType
  70. Private TempDist As CodesType
  71. Private LenOrder(18) As Long
  72. Private MinLLenght As Long
  73. Private MaxLLenght As Long
  74. Private MinDLenght As Long
  75. Private MaxDLenght As Long
  76. Private IsStaticBuild As Boolean
  77. Private BPPprivat As Long
  78. Private m_width As Long
  79. Private m_height As Long
  80. Private m_bitdepht As Long
  81. Private m_colortype As Long
  82. Private m_compression As Long
  83. Private m_filter As Long
  84. Private m_interlacing As Long
  85. Private m_ErrorNumber As Long
  86. Private m_sAlpha As Boolean
  87. Private m_hAlpha As Boolean
  88. Private trns() As Byte
  89. Private m_hTrans As Boolean
  90. Private m_sTrans As Boolean
  91. Private Colorused As Long
  92. Private bkgd() As Byte
  93. Private m_hbkgd As Boolean
  94. Private m_bkgdColor As Long
  95. Private m_text As String
  96. Private m_Time As String
  97. Private m_ztext As String
  98. Private m_gama As Long
  99. Private m_Bgx As Long
  100. Private m_Bgy As Long
  101. Private m_BGPic As Object
  102. Private m_OwnBkgnd As Boolean
  103. Private m_OBCol As Long
  104. Private m_PicBox As Object
  105. Private m_settoBG As Boolean
  106. Public Function OpenPNG(filename As String) As Long
  107. Dim Stand As Long
  108. Dim Ende As Boolean
  109. Dim Filenumber As Long
  110. Dim Signature(7) As Byte
  111. Dim Test As Long
  112. Dim LΣnge As Long
  113. Dim ChunkName As String * 4
  114. Dim ChunkInhalt() As Byte
  115. Dim CRC32Inhalt As Long
  116. Dim Teststring As String
  117. 'Dim crc32test As New clsCRC
  118. Dim TestCRC32 As Long
  119. Dim Testint As Integer
  120. m_hbkgd = False
  121. m_hTrans = False
  122. BPPprivat = 0
  123. ReDim IDATData(0)
  124. IdataLen = 0
  125. Filenumber = FreeFile
  126. Open filename For Binary As Filenumber
  127. Get Filenumber, , Signature
  128. Test = IsValidSignature(Signature)
  129. If Test <> -1 Then
  130.  m_ErrorNumber = 1
  131.  Exit Function
  132. End If
  133. Do While Ende = False
  134. Get Filenumber, , LΣnge
  135. SwapBytesLong LΣnge
  136. Get Filenumber, , ChunkName
  137. If LΣnge > 0 Then ReDim ChunkInhalt(LΣnge - 1)
  138. Stand = Seek(Filenumber)
  139. If Stand + LΣnge > LOF(Filenumber) Then
  140.  m_ErrorNumber = 3
  141.  Exit Function
  142. End If
  143. Get Filenumber, , ChunkInhalt
  144. Get Filenumber, , CRC32Inhalt
  145. 'SwapBytesLong CRC32Inhalt
  146. 'teststring = ChunkName & StrConv(ChunkInhalt, vbUnicode)
  147. 'Testcrc32 = CRC32(teststring) 'reiner VB-Code
  148. 'crc32test.Algorithm = 1
  149. 'TestCRC32 = crc32test.CalculateString(teststring) 'VB und Assembler
  150. 'If CRC32Inhalt <> 0 Then
  151. 'If CRC32Inhalt <> TestCRC32 Then
  152. 'MsgBox "Bad crc32"
  153. 'm_ErrorNumber = 2
  154. 'Exit Function
  155. 'End If
  156. 'End If
  157. Select Case ChunkName
  158. Case "IHDR"
  159. ReadIHDR ChunkInhalt
  160. Case "PLTE"
  161. ReDim Palettenbyte(UBound(ChunkInhalt))
  162. CopyMemory Palettenbyte(0), ChunkInhalt(0), UBound(ChunkInhalt) + 1
  163. Case "IDAT"
  164. ReDim Preserve IDATData(IdataLen + UBound(ChunkInhalt))
  165. CopyMemory IDATData(IdataLen), ChunkInhalt(0), UBound(ChunkInhalt) + 1
  166. IdataLen = UBound(IDATData) + 1
  167. Case "IEND"
  168. Ende = True
  169. Case "bKGD"
  170. bkgd = ChunkInhalt
  171. ReadBkgd
  172. m_hbkgd = True
  173. Case "cHRM"
  174. Case "oFFs"
  175. Case "pCaL"
  176. Case "sCAL"
  177. Case "gAMA"
  178. CopyMemory ByVal VarPtr(m_gama), ChunkInhalt(0), 4
  179. SwapBytesLong m_gama
  180. Case "hIST"
  181. Case "pHYs"
  182. Case "sBIT"
  183. Case "tEXt"
  184. m_text = m_text & StrConv(ChunkInhalt, vbUnicode) & Chr(0)
  185. Case "zTXt"
  186. DecompressText ChunkInhalt
  187. Case "gIFg"
  188. Case "gIFx"
  189. Case "tIME"
  190. CopyMemory ByVal VarPtr(Testint), ChunkInhalt(0), 2
  191. Swap Testint
  192. m_Time = Format(ChunkInhalt(3), "00") & "." & Format(ChunkInhalt(2), "00") & "." & Testint & " " & Format(ChunkInhalt(4), "00") & ":" & Format(ChunkInhalt(5), "00") & ":" & Format(ChunkInhalt(6), "00")
  193. Case "tRNS"
  194. m_hTrans = True
  195. trns = ChunkInhalt
  196. Case "cTXt"
  197. Case Else
  198. 'If Asc(Left(ChunkName, 1)) > 65 Then Exit Function 'kritischer Chunk
  199. End Select
  200. Loop
  201. If IdataLen = 0 Then
  202. m_ErrorNumber = 4
  203. Exit Function
  204. End If
  205. Close Filenumber
  206. MakePicture
  207. End Function
  208. Private Function IsValidSignature(Signature() As Byte) As Boolean
  209. If Signature(0) <> 137 Then Exit Function
  210. If Signature(1) <> 80 Then Exit Function
  211. If Signature(2) <> 78 Then Exit Function
  212. If Signature(3) <> 71 Then Exit Function
  213. If Signature(4) <> 13 Then Exit Function
  214. If Signature(5) <> 10 Then Exit Function
  215. If Signature(6) <> 26 Then Exit Function
  216. If Signature(7) <> 10 Then Exit Function
  217.  IsValidSignature = True
  218. End Function
  219. Private Sub SwapBytesLong(ByteValue As Long)
  220. Dim ▄bergabe As Long
  221. Dim i As Long
  222. For i = 0 To 3
  223. CopyMemory ByVal VarPtr(▄bergabe) + i, ByVal VarPtr(ByteValue) + (3 - i), 1
  224. Next i
  225. ByteValue = ▄bergabe
  226. End Sub
  227. Private Sub ReadIHDR(Bytefeld() As Byte)
  228. Dim Header As IHDR
  229. CopyMemory ByVal VarPtr(Header), Bytefeld(0), 13
  230. SwapBytesLong Header.Width
  231. SwapBytesLong Header.Height
  232. m_width = Header.Width
  233. m_height = Header.Height
  234. m_bitdepht = Header.BitDepth
  235. m_colortype = Header.ColorType
  236. m_compression = Header.Compression
  237. m_filter = Header.Filter
  238. m_interlacing = Header.Interlacing
  239. End Sub
  240. Public Property Get Width() As Long
  241. Width = m_width
  242. End Property
  243. Public Property Get Height() As Long
  244. Height = m_height
  245. End Property
  246. Public Property Get Bitdepht() As Long
  247. Bitdepht = m_bitdepht
  248. End Property
  249. Public Property Get ColorType() As Long
  250. ColorType = m_colortype
  251. End Property
  252. Public Property Get Compression() As Long
  253. Compression = m_compression
  254. End Property
  255. Public Property Get Filter() As Long
  256. Filter = m_filter
  257. End Property
  258. Public Property Get Interlacing() As Long
  259. Interlacing = m_interlacing
  260. End Property
  261. Private Sub MakePicture()
  262. Dim DataSize As Long
  263. Dim Buffer() As Byte
  264. Dim BitCount As Integer
  265. Dim Bitdepht As Long
  266. Dim Drehen As Integer
  267. m_hAlpha = False
  268. Drehen = 1
  269. Select Case Me.Interlacing
  270. Case 0
  271.  DataSize = DataPerRow * Me.Height
  272. Case 1
  273.  DataSize = (DataPerRow * Me.Height) + Me.Height
  274. End Select
  275.  ReDim Buffer(UBound(IDATData) - 2)
  276.  CopyMemory Buffer(0), IDATData(2), UBound(IDATData) - 1
  277. Select Case Me.Compression
  278. Case 0
  279.  Decompress Buffer, DataSize
  280. End Select
  281. Select Case Me.Interlacing
  282. Case 0
  283.  Buffer = DeFilter(Buffer)
  284.  Drehen = 1
  285. Case 1
  286.  Buffer = DeFilterInterlaced(Buffer)
  287.  Drehen = 0
  288. End Select
  289.  BitCount = Me.Bitdepht
  290. Select Case Me.ColorType
  291. Case 0 'Grayscale
  292. Select Case Me.Bitdepht
  293. Case 16
  294.  Conv16To8 Buffer
  295.  InitColorTable_Grey 8
  296.  BitCount = 8
  297.  BPPprivat = 8
  298. Case 8, 4, 1
  299. Select Case Interlacing
  300. Case 0
  301.  BitCount = Me.Bitdepht
  302.  InitColorTable_Grey Me.Bitdepht, False
  303.  Align32 BitCount, Buffer
  304. Case Else
  305.  BitCount = 8
  306.  InitColorTable_Grey Me.Bitdepht, True
  307. End Select
  308. Case 2
  309.  InitColorTable_Grey 2
  310. If Me.Interlacing = 0 Then
  311.  Pal2To8 Me.Width, Me.Height, Buffer, DataPerRow
  312. End If
  313.  BitCount = 8
  314.  BPPprivat = 8
  315. End Select
  316. If m_hTrans And m_sTrans Then
  317. If Me.Bitdepht <> 2 Then
  318.  Align32 BitCount, Buffer
  319. End If
  320.  PalToRGBA Me.Width, Me.Height, BitCount, Buffer
  321.  BitCount = 32
  322.  BPPprivat = 32
  323.  MakeAlpha m_BGPic, Buffer, m_Bgx, m_Bgy
  324.  BitCount = 24
  325.  BPPprivat = 24
  326. End If
  327. Case 2 'RGB
  328. If Me.Bitdepht = 16 Then Conv16To8 Buffer
  329.  BitCount = 24
  330.  BPPprivat = 24
  331.  ReverseRGB Buffer
  332.  Drehen = 1
  333.  BPPprivat = 8
  334.  Align32 BitCount, Buffer
  335.  BPPprivat = 24
  336. If m_hTrans And m_sTrans Then
  337.  MakeRGBTransparent Buffer
  338.  MirrorData Buffer, Me.Width * 4
  339.  Drehen = 0
  340.  BitCount = 32
  341.  BPPprivat = 32
  342.  MakeAlpha m_BGPic, Buffer, m_Bgx, m_Bgy
  343.  BitCount = 24
  344.  BPPprivat = 24
  345. End If
  346. Case 3 'Palette
  347. Select Case Me.Bitdepht
  348. Case 8, 4, 1
  349. If Me.Interlacing = 1 Then
  350.  BitCount = 8
  351.  BPPprivat = 8
  352.  Align32 BitCount, Buffer
  353. Else
  354.  BitCount = Me.Bitdepht
  355. If BitCount >= 8 Then
  356.  Align32 BitCount, Buffer
  357. End If
  358. End If
  359. Case 2
  360. If Me.Interlacing = 0 Then
  361.  Pal2To8 Me.Width, Me.Height, Buffer, DataPerRow
  362.  BitCount = 8
  363.  BPPprivat = 8
  364. Else
  365.  BitCount = 8
  366.  BPPprivat = 8
  367.  Align32 BitCount, Buffer
  368. End If
  369. End Select
  370. If m_hTrans And m_sTrans Then
  371. If Me.Bitdepht <> 2 Then
  372.  Align32 BitCount, Buffer
  373. End If
  374.  PalToRGBA Me.Width, Me.Height, BitCount, Buffer
  375.  BitCount = 32
  376.  BPPprivat = 32
  377.  MakeAlpha m_BGPic, Buffer, m_Bgx, m_Bgy
  378.  BitCount = 24
  379.  BPPprivat = 24
  380. End If
  381. Case 4 'Grayscale + Alpha
  382.  m_hAlpha = True
  383. If Me.Bitdepht = 16 Then Conv16To8 Buffer
  384.  GrayAToRGBA Buffer
  385.  BPPprivat = 32
  386.  BitCount = 32
  387.  MirrorData Buffer, LineBytes(Me.Width, BitCount)
  388.  Drehen = 0
  389. If m_sAlpha = True Then
  390.  MakeAlpha m_BGPic, Buffer, m_Bgx, m_Bgy
  391.  BPPprivat = 24
  392.  BitCount = 24
  393. End If
  394. Case 6 'RGB + Alpha
  395.  m_hAlpha = True
  396. If Me.Bitdepht = 16 Then Conv16To8 Buffer
  397.  BitCount = 32
  398.  BPPprivat = 32
  399.  ReverseRGBA Buffer
  400.  MirrorData Buffer, LineBytes(Me.Width, BitCount)
  401.  Drehen = 0
  402. If m_sAlpha = True Then
  403.  MakeAlpha m_BGPic, Buffer, m_Bgx, m_Bgy
  404.  BPPprivat = 24
  405.  BitCount = 24
  406. End If
  407. End Select
  408. If Not (((Me.ColorType = 3) And (BitCount = 32)) Or _
  409.  (Me.Bitdepht = 2)) Then
  410. Select Case Me.Bitdepht
  411. Case 16
  412.  Bitdepht = 8
  413.  Bitdepht = 16
  414. End Select
  415. End If
  416. Select Case BitCount
  417. Case 1, 2, 4
  418.  Align32 BitCount, Buffer
  419. End Select
  420. Select Case BitCount
  421. Case 1
  422. Select Case Me.ColorType
  423. Case 3
  424.  InitColorTable_1Palette Palettenbyte
  425. Case Else
  426.  InitColorTable_1
  427. End Select
  428.  CreateBitmap_1 Buffer, Me.Width, Me.Height, True, Colorused
  429.  DrawBitmap Me.Width, Me.Height, m_PicBox, True, m_Bgx, m_Bgy, m_settoBG
  430. Case 4
  431. Select Case Me.ColorType
  432. Case 0
  433. Case Else
  434.  InitColorTable_4 Palettenbyte
  435. End Select
  436.  CreateBitmap_4 Buffer, Me.Width, Me.Height, True, Colorused
  437.  DrawBitmap Me.Width, Me.Height, m_PicBox, True, m_Bgx, m_Bgy, m_settoBG
  438. Case 8
  439. Select Case Me.ColorType
  440. Case 0, 4
  441. Case Else
  442.  InitColorTable_8 Palettenbyte
  443. End Select
  444.  Drehen = 1
  445.  CreateBitmap_8 Buffer, Me.Width, Me.Height, Drehen, Colorused
  446.  DrawBitmap Me.Width, Me.Height, m_PicBox, True, m_Bgx, m_Bgy, m_settoBG
  447. Case 24
  448.  CreateBitmap_24 Buffer, Me.Width, Me.Height, Drehen, 1
  449.  DrawBitmap Me.Width, Me.Height, m_PicBox, True, m_Bgx, m_Bgy, m_settoBG
  450. Case 32
  451.  CreateBitmap_24 Buffer, Me.Width, Me.Height, Drehen
  452.  DrawBitmap Me.Width, Me.Height, m_PicBox, True, m_Bgx, m_Bgy, m_settoBG
  453. End Select
  454. End Sub
  455. Private Function Decompress(ByteArray() As Byte, UncompressedSize As Long, Optional ZIP64 As Boolean = False) As Long
  456. Dim IsLastBlock As Boolean
  457. Dim CompType As Long
  458. Dim Char As Long
  459. Dim Nubits As Long
  460. Dim L1 As Long
  461. Dim L2 As Long
  462. Dim x As Long
  463. UncompressedSize = UncompressedSize + 100
  464. InStream = ByteArray
  465. Call Init_Decompress(UncompressedSize)
  466. Do
  467.  IsLastBlock = GetBits(1)
  468.  CompType = GetBits(2)
  469. If CompType = 0 Then
  470. If Inpos + 4 > UBound(InStream) Then
  471.  Decompress = -1
  472.  Exit Do
  473. End If
  474. Do While BitNum >= 8
  475.  Inpos = Inpos - 1
  476.  BitNum = BitNum - 8
  477. Loop
  478.  CopyMemory L1, InStream(Inpos), 2&
  479.  CopyMemory L2, InStream(Inpos + 2), 2&
  480.  Inpos = Inpos + 4
  481. If L1 - (Not (L2) And &HFFFF&) Then Decompress = -2
  482. If Inpos + L1 - 1 > UBound(InStream) Then
  483.  Decompress = -1
  484.  Exit Do
  485. End If
  486. If OutPos + L1 - 1 > UBound(OutStream) Then
  487.  Decompress = -1
  488.  Exit Do
  489. End If
  490.  CopyMemory OutStream(OutPos), InStream(Inpos), L1
  491.  OutPos = OutPos + L1
  492.  Inpos = Inpos + L1
  493.  ByteBuff = 0
  494.  BitNum = 0
  495. ElseIf CompType = 3 Then
  496.  Decompress = -1
  497.  Exit Do
  498. Else
  499. If CompType = 1 Then
  500. If Create_Static_Tree <> 0 Then
  501.  MsgBox "Error in tree creation (Static)"
  502.  Exit Function
  503. End If
  504. Else
  505. If Create_Dynamic_Tree <> 0 Then
  506.  MsgBox "Error in tree creation (Static)"
  507.  Exit Function
  508. End If
  509. End If
  510.  Do
  511.  NeedBits MaxLLenght
  512.  Nubits = MinLLenght
  513. Do While LitLen.Lenght(ByteBuff And BitMask(Nubits)) <> Nubits
  514.  Nubits = Nubits + 1
  515. Loop
  516.  Char = LitLen.code(ByteBuff And BitMask(Nubits))
  517.  DropBits Nubits
  518. If Char < 256 Then
  519.  OutStream(OutPos) = Char
  520.  OutPos = OutPos + 1
  521. ElseIf Char > 256 Then
  522.  Char = Char - 257
  523.  L1 = LC.code(Char) + GetBits(LC.Lenght(Char))
  524. If (L1 = 258) And ZIP64 Then L1 = GetBits(16) + 3
  525.  NeedBits MaxDLenght
  526.  Nubits = MinDLenght
  527. Do While Dist.Lenght(ByteBuff And BitMask(Nubits)) <> Nubits
  528.  Nubits = Nubits + 1
  529. Loop
  530.  Char = Dist.code(ByteBuff And BitMask(Nubits))
  531.  DropBits Nubits
  532.  L2 = dc.code(Char) + GetBits(dc.Lenght(Char))
  533. For x = 1 To L1
  534. If OutPos > UncompressedSize Then
  535.  OutPos = UncompressedSize
  536.  GoTo Stop_Decompression
  537. End If
  538.  OutStream(OutPos) = OutStream(OutPos - L2)
  539.  OutPos = OutPos + 1
  540. Next x
  541. End If
  542. Loop While Char <> 256 'EOB
  543. End If
  544. Loop While Not IsLastBlock
  545. Stop_Decompression:
  546. If OutPos > 0 Then
  547.  ReDim Preserve OutStream(OutPos - 1)
  548. Else
  549.  Erase OutStream
  550. End If
  551. Erase InStream
  552. Erase BitMask
  553. Erase Pow2
  554. Erase LC.code
  555. Erase LC.Lenght
  556. Erase dc.code
  557. Erase dc.Lenght
  558. Erase LitLen.code
  559. Erase LitLen.Lenght
  560. Erase Dist.code
  561. Erase Dist.Lenght
  562. Erase LenOrder
  563. ByteArray = OutStream
  564. End Function
  565. Private Function Create_Static_Tree()
  566. Dim x As Long
  567. Dim Lenght(287) As Long
  568. If IsStaticBuild = False Then
  569. For x = 0 To 143: Lenght(x) = 8: Next
  570. For x = 144 To 255: Lenght(x) = 9: Next
  571. For x = 256 To 279: Lenght(x) = 7: Next
  572. For x = 280 To 287: Lenght(x) = 8: Next
  573. If Create_Codes(TempLit, Lenght, 287, MaxLLenght, MinLLenght) <> 0 Then
  574.  Create_Static_Tree = -1
  575.  Exit Function
  576. End If
  577. For x = 0 To 31: Lenght(x) = 5: Next
  578.  Create_Static_Tree = Create_Codes(TempDist, Lenght, 31, MaxDLenght, MinDLenght)
  579.  IsStaticBuild = True
  580. Else
  581.  MinLLenght = 7
  582.  MaxLLenght = 9
  583.  MinDLenght = 5
  584.  MaxDLenght = 5
  585. End If
  586. LitLen = TempLit
  587. Dist = TempDist
  588. End Function
  589. Private Function Create_Dynamic_Tree() As Long
  590. Dim Lenght() As Long
  591. Dim Bl_Tree As CodesType
  592. Dim MinBL As Long
  593. Dim MaxBL As Long
  594. Dim NumLen As Long
  595. Dim Numdis As Long
  596. Dim NumCod As Long
  597. Dim Char As Long
  598. Dim Nubits As Long
  599. Dim LN As Long
  600. Dim Pos As Long
  601. Dim x As Long
  602. NumLen = GetBits(5) + 257
  603. Numdis = GetBits(5) + 1
  604. NumCod = GetBits(4) + 4
  605. ReDim Lenght(18)
  606. For x = 0 To NumCod - 1
  607.  Lenght(LenOrder(x)) = GetBits(3)
  608. Next
  609. For x = NumCod To 18
  610.  Lenght(LenOrder(x)) = 0
  611. Next
  612. If Create_Codes(Bl_Tree, Lenght, 18, MaxBL, MinBL) <> 0 Then
  613.  Create_Dynamic_Tree = -1
  614.  Exit Function
  615. End If
  616. ReDim Lenght(NumLen + Numdis)
  617. Pos = 0
  618. Do While Pos < NumLen + Numdis
  619.  NeedBits MaxBL
  620.  Nubits = MinBL
  621. Do While Bl_Tree.Lenght(ByteBuff And BitMask(Nubits)) <> Nubits
  622.  Nubits = Nubits + 1
  623. Loop
  624.  Char = Bl_Tree.code(ByteBuff And BitMask(Nubits))
  625.  DropBits Nubits
  626. If Char < 16 Then
  627.  Lenght(Pos) = Char
  628.  Pos = Pos + 1
  629. Else
  630. If Char = 16 Then
  631. If Pos = 0 Then
  632.  Create_Dynamic_Tree = -5
  633.  Exit Function
  634. End If
  635.  LN = Lenght(Pos - 1)
  636.  Char = 3 + GetBits(2)
  637. ElseIf Char = 17 Then
  638.  Char = 3 + GetBits(3)
  639.  LN = 0
  640. Else
  641.  Char = 11 + GetBits(7)
  642.  LN = 0
  643. End If
  644. If Pos + Char > NumLen + Numdis Then
  645.  Create_Dynamic_Tree = -6
  646.  Exit Function
  647. End If
  648. Do While Char > 0
  649.  Char = Char - 1
  650.  Lenght(Pos) = LN
  651.  Pos = Pos + 1
  652. Loop
  653. End If
  654. Loop
  655. If Create_Codes(LitLen, Lenght, NumLen - 1, MaxLLenght, MinLLenght) <> 0 Then
  656.  Create_Dynamic_Tree = -1
  657.  Exit Function
  658. End If
  659. For x = 0 To Numdis
  660.  Lenght(x) = Lenght(x + NumLen)
  661. Next
  662.  Create_Dynamic_Tree = Create_Codes(Dist, Lenght, Numdis - 1, MaxDLenght, MinDLenght)
  663. End Function
  664. Private Function Create_Codes(tree As CodesType, Lenghts() As Long, NumCodes As Long, MaxBits As Long, Minbits As Long) As Long
  665. Dim Bits(16) As Long
  666. Dim next_code(16) As Long
  667. Dim code As Long
  668. Dim LN As Long
  669. Dim x As Long
  670. Minbits = 16
  671. For x = 0 To NumCodes
  672.  Bits(Lenghts(x)) = Bits(Lenghts(x)) + 1
  673. If Lenghts(x) > MaxBits Then MaxBits = Lenghts(x)
  674. If Lenghts(x) < Minbits And Lenghts(x) > 0 Then Minbits = Lenghts(x)
  675. Next
  676. LN = 1
  677. For x = 1 To MaxBits
  678.  LN = LN + LN
  679.  LN = LN - Bits(x)
  680. If LN < 0 Then Create_Codes = LN: Exit Function
  681. Next
  682. Create_Codes = LN
  683. ReDim tree.code(2 ^ MaxBits - 1)
  684. ReDim tree.Lenght(2 ^ MaxBits - 1)
  685. code = 0
  686. Bits(0) = 0
  687. For x = 1 To MaxBits
  688.  code = (code + Bits(x - 1)) * 2
  689. next_code(x) = code
  690. Next
  691. For x = 0 To NumCodes
  692.  LN = Lenghts(x)
  693. If LN <> 0 Then
  694.  code = Bit_Reverse(next_code(LN), LN)
  695.  tree.Lenght(code) = LN
  696.  tree.code(code) = x
  697. next_code(LN) = next_code(LN) + 1
  698. End If
  699. Next
  700. End Function
  701. Private Function Bit_Reverse(ByVal Value As Long, ByVal Numbits As Long)
  702. Do While Numbits > 0
  703.  Bit_Reverse = Bit_Reverse * 2 + (Value And 1)
  704.  Numbits = Numbits - 1
  705.  Value = Value \ 2
  706. Loop
  707. End Function
  708. Private Sub Init_Decompress(UncompressedSize As Long)
  709. Dim Temp()
  710. Dim x As Long
  711. ReDim OutStream(UncompressedSize)
  712. Erase LitLen.code
  713. Erase LitLen.Lenght
  714. Erase Dist.code
  715. Erase Dist.Lenght
  716. ReDim LC.code(31)
  717. ReDim LC.Lenght(31)
  718. ReDim dc.code(31)
  719. ReDim dc.Lenght(31)
  720. Temp() = Array(16, 17, 18, 0, 8, 7, 9, 6, 10, 5, 11, 4, 12, 3, 13, 2, 14, 1, 15)
  721. For x = 0 To UBound(Temp): LenOrder(x) = Temp(x): Next
  722.  Temp() = Array(3, 4, 5, 6, 7, 8, 9, 10, 11, 13, 15, 17, 19, 23, 27, 31, 35, 43, 51, 59, 67, 83, 99, 115, 131, 163, 195, 227, 258)
  723. For x = 0 To UBound(Temp): LC.code(x) = Temp(x): Next
  724.  Temp() = Array(0, 0, 0, 0, 0, 0, 0, 0, 1, 1, 1, 1, 2, 2, 2, 2, 3, 3, 3, 3, 4, 4, 4, 4, 5, 5, 5, 5, 0)
  725. For x = 0 To UBound(Temp): LC.Lenght(x) = Temp(x): Next
  726.  Temp() = Array(1, 2, 3, 4, 5, 7, 9, 13, 17, 25, 33, 49, 65, 97, 129, 193, 257, 385, 513, 769, 1025, 1537, 2049, 3073, 4097, 6145, 8193, 12289, 16385, 24577, 32769, 49153)
  727. For x = 0 To UBound(Temp): dc.code(x) = Temp(x): Next
  728.  Temp() = Array(0, 0, 0, 0, 1, 1, 2, 2, 3, 3, 4, 4, 5, 5, 6, 6, 7, 7, 8, 8, 9, 9, 10, 10, 11, 11, 12, 12, 13, 13, 14, 14)
  729. For x = 0 To UBound(Temp): dc.Lenght(x) = Temp(x): Next
  730. For x = 0 To 16
  731.  BitMask(x) = 2 ^ x - 1
  732.  Pow2(x) = 2 ^ x
  733. Next
  734. OutPos = 0
  735. Inpos = 0
  736. ByteBuff = 0
  737. BitNum = 0
  738. End Sub
  739. Private Sub PutByte(Char As Byte)
  740. If OutPos > UBound(OutStream) Then ReDim Preserve OutStream(OutPos + 1000)
  741. OutStream(OutPos) = Char
  742. OutPos = OutPos + 1
  743. End Sub
  744. Private Sub NeedBits(Numbits As Long)
  745. While BitNum < Numbits
  746. If Inpos > UBound(InStream) Then Exit Sub
  747.  ByteBuff = ByteBuff + (InStream(Inpos) * Pow2(BitNum))
  748.  BitNum = BitNum + 8
  749.  Inpos = Inpos + 1
  750.  Wend
  751. End Sub
  752. Private Sub DropBits(Numbits As Long)
  753. ByteBuff = ByteBuff \ Pow2(Numbits)
  754. BitNum = BitNum - Numbits
  755. End Sub
  756. Private Function GetBits(Numbits As Long) As Long
  757. While BitNum < Numbits
  758.  ByteBuff = ByteBuff + (InStream(Inpos) * Pow2(BitNum))
  759.  BitNum = BitNum + 8
  760.  Inpos = Inpos + 1
  761. Wend
  762. GetBits = ByteBuff And BitMask(Numbits)
  763. ByteBuff = ByteBuff \ Pow2(Numbits)
  764. BitNum = BitNum - Numbits
  765. End Function
  766. Private Function DeFilter(Dat() As Byte) As Byte()
  767. Dim NewDat() As Byte, y As Long, iVal As Long
  768. Dim n As Long, StartByte As Long, DestByte As Long
  769. Dim BPRow As Long, x As Long, RowBytes() As Byte
  770. Dim PrevRowBytes() As Byte
  771. Dim i As Long
  772. iVal = Interval()
  773. BPRow = DataPerRow()
  774. ReDim NewDat(UBound(Dat) - Me.Height)
  775. ReDim PrevRowBytes(DataPerRow() - 2)
  776. ReDim RowBytes(DataPerRow() - 2)
  777. For y = 0 To Me.Height - 1
  778.  StartByte = BPRow * y
  779.  DestByte = StartByte - y
  780.  x = 0
  781.  CopyMemory RowBytes(0), Dat(StartByte + 1), BPRow - 1
  782. Select Case Dat(StartByte)
  783. Case 0 'None
  784. Case 1 'Sub
  785.  ReverseSub RowBytes, iVal
  786. Case 2 'Up
  787.  ReverseUp RowBytes, PrevRowBytes
  788. Case 3 'Average
  789.  ReverseAverage RowBytes, PrevRowBytes, iVal
  790. Case 4 'Paeth
  791.  ReversePaeth RowBytes, PrevRowBytes, iVal
  792. End Select
  793.  CopyMemory NewDat(DestByte), RowBytes(0), BPRow - 1
  794.  PrevRowBytes = RowBytes
  795. Next y
  796. DeFilter = NewDat
  797. End Function
  798. Private Function Interval() As Long
  799. Interval = BitsPerPixel() \ 8
  800. If Interval = 0 Then Interval = 1
  801. End Function
  802. Private Function BitsPerPixel() As Long
  803. Dim Bpp As Long
  804. If RBD = 0 Then
  805.  Bpp = Me.Bitdepht
  806. Else
  807.  Bpp = RBD
  808. End If
  809. If BPPprivat <> Bpp And BPPprivat <> 0 Then Bpp = BPPprivat
  810. Select Case Me.ColorType
  811. Case 0, 3: BitsPerPixel = Bpp
  812. Case 2: BitsPerPixel = 3 * Bpp
  813. Case 6: BitsPerPixel = 4 * Bpp
  814. Case 4: BitsPerPixel = 2 * Bpp
  815. End Select
  816. End Function
  817. Private Function DataPerRow() As Long
  818. DataPerRow = (Me.Width * BitsPerPixel() + 7) \ 8 + 1
  819. End Function
  820. Private Sub ReverseAverage(CurRow() As Byte, PrevRow() As Byte, Interval As Long)
  821. Dim PrevOff As Long, PrevVal As Byte, BPRow As Long
  822. Dim n As Long, x As Integer
  823. BPRow = UBound(CurRow) + 1
  824. For n = 0 To BPRow - 1
  825.  PrevOff = n - Interval
  826. If PrevOff >= 0 Then
  827.  PrevVal = CurRow(PrevOff)
  828. End If
  829.  x = CurRow(n) + (CInt(PrevRow(n)) + CInt(PrevVal)) \ 2
  830.  CopyMemory CurRow(n), x, 1
  831. Next n
  832. End Sub
  833. Private Sub ReversePaeth(CurRow() As Byte, PrevRow() As Byte, Interval As Long)
  834. Dim BPRow As Long, n As Long, x As Integer
  835. Dim LeftPixOff As Long, LeftPix As Byte
  836. Dim UpperLeftPix As Byte
  837. BPRow = UBound(CurRow) + 1
  838. For n = 0 To BPRow - 1
  839.  LeftPixOff = n - Interval
  840. If LeftPixOff >= 0 Then
  841.  LeftPix = CurRow(LeftPixOff)
  842.  UpperLeftPix = PrevRow(LeftPixOff)
  843. End If
  844.  x = CInt(CurRow(n)) + CInt(PaethPredictor(LeftPix, PrevRow(n), UpperLeftPix))
  845.  CopyMemory CurRow(n), x, 1
  846. Next n
  847. End Sub
  848. Private Sub ReverseUp(CurRow() As Byte, PrevRow() As Byte)
  849. Dim PrevVal As Byte, BPRow As Long
  850. Dim n As Long, x As Integer
  851.  BPRow = UBound(CurRow) + 1
  852. For n = 0 To BPRow - 1
  853.  PrevVal = PrevRow(n)
  854.  x = CInt(CurRow(n)) + CInt(PrevVal)
  855.  CopyMemory CurRow(n), x, 1
  856. Next n
  857. End Sub
  858. Private Sub ReverseSub(CurRow() As Byte, Interval As Long)
  859. Dim PrevOff As Long, PrevVal As Byte, BPRow As Long
  860. Dim n As Long, x As Integer
  861. BPRow = UBound(CurRow) + 1
  862. For n = 0 To BPRow - 1
  863.  PrevOff = n - Interval
  864. If PrevOff >= 0 Then
  865.  PrevVal = CurRow(PrevOff)
  866. End If
  867.  x = CInt(CurRow(n)) + CInt(PrevVal)
  868.  CopyMemory CurRow(n), x, 1
  869. Next n
  870. End Sub
  871. Private Function PaethPredictor(Left As Byte, Above As Byte, UpperLeft As Byte) As Byte
  872. Dim pA As Integer, pB As Integer, pC As Integer, p As Integer
  873. p = CInt(Left) + CInt(Above) - CInt(UpperLeft)
  874. pA = Abs(p - Left)
  875. pB = Abs(p - Above)
  876. pC = Abs(p - UpperLeft)
  877. If (pA <= pB) And (pA <= pC) Then
  878.  PaethPredictor = Left
  879. ElseIf pB <= pC Then
  880.  PaethPredictor = Above
  881. Else
  882.  PaethPredictor = UpperLeft
  883. End If
  884. End Function
  885. Private Sub ReverseRGB(Dat() As Byte)
  886. Dim n As Long, Tmp As Byte
  887. On Error Resume Next
  888. For n = 0 To UBound(Dat) Step 3
  889.  Tmp = Dat(n)
  890.  Dat(n) = Dat(n + 2)
  891.  Dat(n + 2) = Tmp
  892. Next n
  893. End Sub
  894. Private Sub Conv16To8(Dat() As Byte)
  895. Dim n As Long, DestDat() As Byte, DestOff As Long
  896. ReDim DestDat((UBound(Dat) + 1) \ 2 - 1)
  897. For n = 0 To UBound(Dat) Step 2
  898.  DestDat(DestOff) = Dat(n)
  899.  DestOff = DestOff + 1
  900. Next n
  901. Dat = DestDat
  902. End Sub
  903. Private Sub Align32(BitCount As Integer, Dat() As Byte)
  904. Dim RowBytes As Long, SrcRowBytes As Long
  905. Dim y As Long, Dest() As Byte
  906. Dim SrcOff As Long, DestOff As Long
  907. If BitCount = 32 Then Exit Sub
  908.  RowBytes = LineBytes(Me.Width, BitCount)
  909.  SrcRowBytes = DataPerRow() - 1
  910. Select Case Me.ColorType
  911. Case 4 'Alpha
  912.  SrcRowBytes = SrcRowBytes / 2
  913. End Select
  914. If RowBytes = SrcRowBytes Then
  915.  Exit Sub
  916. Else
  917.  ReDim Dest(RowBytes * Me.Height - 1)
  918. For y = 0 To Me.Height - 1
  919.  SrcOff = y * SrcRowBytes
  920.  DestOff = y * RowBytes
  921.  CopyMemory Dest(DestOff), Dat(SrcOff), SrcRowBytes
  922. Next y
  923.  Dat = Dest
  924. End If
  925. End Sub
  926. Private Function LineBytes(Width As Long, BitCount As Integer) As Long
  927. LineBytes = ((Width * BitCount + 31) \ 32) * 4
  928. End Function
  929. Private Sub ReverseRGBA(Dat() As Byte)
  930. Dim n As Long, Tmp As Byte
  931. For n = 0 To UBound(Dat) Step 4
  932.  Tmp = Dat(n)
  933. If n + 2 > UBound(Dat) Then Exit For
  934.  Dat(n) = Dat(n + 2)
  935.  Dat(n + 2) = Tmp
  936. Next n
  937. End Sub
  938. Private Sub Pal2To8(Width As Long, Height As Long, Dat() As Byte, RowBytes As Long)
  939. Dim DestDat() As Byte, DestRowBytes As Long, n As Long
  940. Dim Px As Byte, DestOff As Long, x As Long, y As Long
  941. DestRowBytes = LineBytes(Width, 8)
  942. ReDim DestDat(DestRowBytes * Height - 1)
  943. For y = 0 To Height - 1
  944.  DestOff = y * DestRowBytes
  945. For x = 0 To Width - 1
  946.  n = y * (RowBytes - 1) + x \ 4
  947. If (x Mod 4) <> 3 Then
  948.  Px = (Dat(n) \ 4 ^ (3 - (x Mod 4))) And 3
  949.  Else
  950.  Px = Dat(n) And 3
  951. End If
  952.  DestDat(DestOff) = Px
  953.  DestOff = DestOff + 1
  954. Next x
  955. Next y
  956. Dat = DestDat
  957. End Sub
  958. Private Sub GrayAToRGBA(Dat() As Byte)
  959. Dim n As Long, DestDat() As Byte, DestOff As Long
  960.  ReDim DestDat((UBound(Dat) + 1) * 2 - 1)
  961. For n = 0 To UBound(Dat) Step 2
  962.  DestDat(DestOff) = Dat(n)
  963.  DestDat(DestOff + 1) = Dat(n)
  964.  DestDat(DestOff + 2) = Dat(n)
  965.  DestDat(DestOff + 3) = Dat(n + 1)
  966.  DestOff = DestOff + 4
  967. Next n
  968. Dat = DestDat
  969. End Sub
  970. Private Function DeFilterInterlaced(Buffer() As Byte) As Byte()
  971. Dim Stand As String
  972. Dim x As Long
  973. Dim y As Long
  974. Dim ZL As Long
  975. Dim Bpp As Long
  976. Dim Bufferstand As Long
  977. Dim Zeilenbuffer() As Byte
  978. Dim Height8 As Long
  979. Dim Rest8 As Long
  980. Dim MengeZeilen As Long
  981. Dim i As Long
  982. Dim Filterbyte As Byte
  983. Dim PrevRowBytes() As Byte
  984. Dim ZwischenBuffer() As Byte
  985. Dim Nr As Long
  986. Dim ZZ As Long
  987. Dim BytesPerPixel As Long
  988. Dim ZLBytes As Long
  989. y = Me.Height
  990. x = Me.Width
  991. Bpp = BitsPerPixel
  992. If Bpp >= 8 Then
  993. BytesPerPixel = Bpp / 8
  994. Else
  995. BytesPerPixel = 1
  996. End If
  997. ReDim ZwischenBuffer((x * y * BytesPerPixel) - 1)
  998. Rest8 = y Mod 8
  999. Height8 = (y - Rest8) / 8
  1000. Stand = "1" 'Durchlauf 1
  1001. ZL = BerechneZeilenlΣnge(x, Bpp, Stand)
  1002. If ZL > 0 Then
  1003. ReDim PrevRowBytes(ZL - 1)
  1004. MengeZeilen = Height8
  1005. If Rest8 > 0 Then
  1006. MengeZeilen = MengeZeilen + 1
  1007. End If
  1008. For i = 1 To MengeZeilen
  1009. ReDim Zeilenbuffer(ZL - 1)
  1010. CopyMemory Zeilenbuffer(0), Buffer(Bufferstand + 1), ZL
  1011. Filterbyte = Buffer(Bufferstand)
  1012. FilterInter Zeilenbuffer, Filterbyte, PrevRowBytes
  1013. Bufferstand = Bufferstand + ZL + 1
  1014. If Bpp < 8 Then
  1015. ZLBytes = BerechneZeilenlΣnge(x, 8, Stand)
  1016. Else
  1017. ZLBytes = 0
  1018. End If
  1019. PutBuffer ZwischenBuffer, Zeilenbuffer, 1, 1, i, ZLBytes
  1020. Next i
  1021. End If
  1022. Stand = "5" 'Durchlauf 2
  1023. ZL = BerechneZeilenlΣnge(x, Bpp, Stand)
  1024. If ZL > 0 Then
  1025. ReDim PrevRowBytes(ZL - 1)
  1026. MengeZeilen = Height8
  1027. If Rest8 > 0 Then
  1028. MengeZeilen = MengeZeilen + 1
  1029. End If
  1030. For i = 1 To MengeZeilen
  1031. ReDim Zeilenbuffer(ZL - 1)
  1032. CopyMemory Zeilenbuffer(0), Buffer(Bufferstand + 1), ZL
  1033. Filterbyte = Buffer(Bufferstand)
  1034. FilterInter Zeilenbuffer, Filterbyte, PrevRowBytes
  1035. Bufferstand = Bufferstand + ZL + 1
  1036. If Bpp < 8 Then
  1037. ZLBytes = BerechneZeilenlΣnge(x, 8, Stand)
  1038. Else
  1039. ZLBytes = 0
  1040. End If
  1041. PutBuffer ZwischenBuffer, Zeilenbuffer, 2, 1, i, ZLBytes
  1042. Next i
  1043. End If
  1044. Stand = "15" 'Durchlauf 3
  1045. ZL = BerechneZeilenlΣnge(x, Bpp, Stand)
  1046. If ZL > 0 Then
  1047. ReDim PrevRowBytes(ZL - 1)
  1048. MengeZeilen = Height8
  1049. If Rest8 > 4 Then
  1050. MengeZeilen = MengeZeilen + 1
  1051. End If
  1052. For i = 1 To MengeZeilen
  1053. ReDim Zeilenbuffer(ZL - 1)
  1054. CopyMemory Zeilenbuffer(0), Buffer(Bufferstand + 1), ZL
  1055. Filterbyte = Buffer(Bufferstand)
  1056. FilterInter Zeilenbuffer, Filterbyte, PrevRowBytes
  1057. Bufferstand = Bufferstand + ZL + 1
  1058. If Bpp < 8 Then
  1059. ZLBytes = BerechneZeilenlΣnge(x, 8, Stand)
  1060. Else
  1061. ZLBytes = 0
  1062. End If
  1063. PutBuffer ZwischenBuffer, Zeilenbuffer, 3, 5, i, ZLBytes
  1064. Next i
  1065. End If
  1066. Stand = "37" 'Durchlauf 4 - Zeile 1 - 2
  1067. ZZ = 1
  1068. ZL = BerechneZeilenlΣnge(x, Bpp, Stand)
  1069. If ZL > 0 Then
  1070. ReDim PrevRowBytes(ZL - 1)
  1071. MengeZeilen = Height8 * 2
  1072. If Rest8 > 0 Then
  1073. MengeZeilen = MengeZeilen + 1
  1074. End If
  1075. If Rest8 > 4 Then
  1076. MengeZeilen = MengeZeilen + 1
  1077. End If
  1078. Nr = 1
  1079. For i = 1 To MengeZeilen
  1080. ReDim Zeilenbuffer(ZL - 1)
  1081. CopyMemory Zeilenbuffer(0), Buffer(Bufferstand + 1), ZL
  1082. Filterbyte = Buffer(Bufferstand)
  1083. FilterInter Zeilenbuffer, Filterbyte, PrevRowBytes
  1084. Bufferstand = Bufferstand + ZL + 1
  1085. If Bpp < 8 Then
  1086. ZLBytes = BerechneZeilenlΣnge(x, 8, Stand)
  1087. Else
  1088. ZLBytes = 0
  1089. End If
  1090. PutBuffer ZwischenBuffer, Zeilenbuffer, 4, Nr, ZZ, ZLBytes
  1091. If Nr = 1 Then
  1092. Nr = 5
  1093. Else
  1094. Nr = 1
  1095. ZZ = ZZ + 1
  1096. End If
  1097. Next i
  1098. End If
  1099. Stand = "1357" 'Durchlauf 5 - Zeile 1 - 2
  1100. ZL = BerechneZeilenlΣnge(x, Bpp, Stand)
  1101. If ZL > 0 Then
  1102. ReDim PrevRowBytes(ZL - 1)
  1103. MengeZeilen = Height8 * 2
  1104. If Rest8 > 2 Then
  1105. MengeZeilen = MengeZeilen + 1
  1106. End If
  1107. If Rest8 > 6 Then
  1108. MengeZeilen = MengeZeilen + 1
  1109. End If
  1110. ZZ = 1
  1111. Nr = 3
  1112. For i = 1 To MengeZeilen
  1113. ReDim Zeilenbuffer(ZL - 1)
  1114. CopyMemory Zeilenbuffer(0), Buffer(Bufferstand + 1), ZL
  1115. Filterbyte = Buffer(Bufferstand)
  1116. FilterInter Zeilenbuffer, Filterbyte, PrevRowBytes
  1117. Bufferstand = Bufferstand + ZL + 1
  1118. If Bpp < 8 Then
  1119. ZLBytes = BerechneZeilenlΣnge(x, 8, Stand)
  1120. Else
  1121. ZLBytes = 0
  1122. End If
  1123. PutBuffer ZwischenBuffer, Zeilenbuffer, 5, Nr, ZZ, ZLBytes
  1124. Select Case Nr
  1125. Case 3
  1126. Nr = 7
  1127. Case 7
  1128. Nr = 3
  1129. ZZ = ZZ + 1
  1130. End Select
  1131. Next i
  1132. End If
  1133. Stand = "2468" 'Durchlauf 6 - Zeile 1 - 4
  1134. ZL = BerechneZeilenlΣnge(x, Bpp, Stand)
  1135. If ZL > 0 Then
  1136. ReDim PrevRowBytes(ZL - 1)
  1137. ZZ = 1
  1138. Nr = 1
  1139. MengeZeilen = Height8 * 4
  1140. If Rest8 > 0 Then
  1141. MengeZeilen = MengeZeilen + 1
  1142. End If
  1143. If Rest8 > 2 Then
  1144. MengeZeilen = MengeZeilen + 1
  1145. End If
  1146. If Rest8 > 4 Then
  1147. MengeZeilen = MengeZeilen + 1
  1148. End If
  1149. If Rest8 > 6 Then
  1150. MengeZeilen = MengeZeilen + 1
  1151. End If
  1152. For i = 1 To MengeZeilen
  1153. ReDim Zeilenbuffer(ZL - 1)
  1154. CopyMemory Zeilenbuffer(0), Buffer(Bufferstand + 1), ZL
  1155. Filterbyte = Buffer(Bufferstand)
  1156. FilterInter Zeilenbuffer, Filterbyte, PrevRowBytes
  1157. Bufferstand = Bufferstand + ZL + 1
  1158. If Bpp < 8 Then
  1159. ZLBytes = BerechneZeilenlΣnge(x, 8, Stand)
  1160. Else
  1161. ZLBytes = 0
  1162. End If
  1163. PutBuffer ZwischenBuffer, Zeilenbuffer, 6, Nr, ZZ, ZLBytes
  1164. Select Case Nr
  1165. Case 1
  1166. Nr = 3
  1167. Case 3
  1168. Nr = 5
  1169. Case 5
  1170. Nr = 7
  1171. Case 7
  1172. Nr = 1
  1173. ZZ = ZZ + 1
  1174. End Select
  1175. Next i
  1176. End If
  1177. Stand = "12345678" 'Durchlauf 7 - Zeile 1 - 4
  1178. ZL = BerechneZeilenlΣnge(x, Bpp, Stand)
  1179. If ZL > 0 Then
  1180. ReDim PrevRowBytes(ZL - 1)
  1181. ZZ = 1
  1182. Nr = 2
  1183. MengeZeilen = Height8 * 4
  1184. If Rest8 > 1 Then
  1185. MengeZeilen = MengeZeilen + 1
  1186. End If
  1187. If Rest8 > 3 Then
  1188. MengeZeilen = MengeZeilen + 1
  1189. End If
  1190. If Rest8 > 5 Then
  1191. MengeZeilen = MengeZeilen + 1
  1192. End If
  1193. If Rest8 > 7 Then
  1194. MengeZeilen = MengeZeilen + 1
  1195. End If
  1196. For i = 1 To MengeZeilen
  1197. ReDim Zeilenbuffer(ZL - 1)
  1198. CopyMemory Zeilenbuffer(0), Buffer(Bufferstand + 1), ZL
  1199. Filterbyte = Buffer(Bufferstand)
  1200. FilterInter Zeilenbuffer, Filterbyte, PrevRowBytes
  1201. Bufferstand = Bufferstand + ZL + 1
  1202. If Bpp < 8 Then
  1203. ZLBytes = BerechneZeilenlΣnge(x, 8, Stand)
  1204. Else
  1205. ZLBytes = 0
  1206. End If
  1207. PutBuffer ZwischenBuffer, Zeilenbuffer, 7, Nr, ZZ, ZLBytes
  1208. Select Case Nr
  1209. Case 2
  1210. Nr = 4
  1211. Case 4
  1212. Nr = 6
  1213. Case 6
  1214. Nr = 8
  1215. Case 8
  1216. Nr = 2
  1217. ZZ = ZZ + 1
  1218. End Select
  1219. Next i
  1220. End If
  1221. DeFilterInterlaced = ZwischenBuffer
  1222. End Function
  1223. Private Function BerechneZeilenlΣnge(x As Long, Bpp As Long, Stand As String) As Long
  1224. Dim Hilfslong As Long
  1225. Dim LΣngenrest As Long
  1226. Dim LΣnge8 As Long
  1227. Dim Testlong As Long
  1228. Dim Anzahl8 As Long
  1229. Dim AnzahlBits As Long
  1230. Dim Bytesrest As Long
  1231. Dim NBytes As Long
  1232. Dim AnzRB As Long
  1233. Dim Rest As Long
  1234. Dim MengeBits As Long
  1235. Dim i As Long
  1236. Dim BiggerAs As Long
  1237. Dim Menge As Long
  1238. MengeBits = Len(Stand)
  1239. LΣngenrest = x Mod 8
  1240. BiggerAs = 0
  1241. Menge = 0
  1242. For i = 1 To MengeBits
  1243. If CLng(Mid(Stand, i, 1)) <= LΣngenrest Then
  1244. Menge = Menge + 1
  1245. Else
  1246. Exit For
  1247. End If
  1248. Next i
  1249. If Bpp < 8 Then
  1250. If LΣngenrest > 0 Then
  1251.  Rest = Bpp * Menge
  1252.  Else
  1253.  Rest = 0
  1254. End If
  1255. Else
  1256. Rest = Menge * (Bpp / 8)
  1257. End If
  1258. Anzahl8 = (x - LΣngenrest) / 8
  1259. AnzahlBits = Anzahl8 * Bpp * MengeBits
  1260. Bytesrest = AnzahlBits Mod 8
  1261. NBytes = (AnzahlBits - Bytesrest) / 8
  1262. Select Case Bpp
  1263. Case Is < 8
  1264. Rest = Rest + Bytesrest
  1265. Testlong = Rest Mod 8
  1266. AnzRB = (Rest - Testlong) / 8
  1267. If Testlong <> 0 Then AnzRB = AnzRB + 1
  1268. BerechneZeilenlΣnge = NBytes + AnzRB
  1269. Case Else
  1270. BerechneZeilenlΣnge = NBytes + Rest
  1271. End Select
  1272. End Function
  1273. Private Sub FilterInter(RowBytes() As Byte, Filterbyte As Byte, PrevRowBytes() As Byte)
  1274. Dim iVal As Long
  1275.  iVal = Interval()
  1276. Select Case Filterbyte
  1277. Case 0 'None
  1278. Case 1 'Sub
  1279.  ReverseSub RowBytes, iVal
  1280. Case 2 'Up
  1281.  ReverseUp RowBytes, PrevRowBytes
  1282. Case 3 'Average
  1283.  ReverseAverage RowBytes, PrevRowBytes, iVal
  1284. Case 4 'Paeth
  1285.  ReversePaeth RowBytes, PrevRowBytes, iVal
  1286. End Select
  1287.  PrevRowBytes = RowBytes
  1288. End Sub
  1289. Private Sub PutBuffer(Buffer() As Byte, Zeilenbuffer() As Byte, Zeilentyp As Byte, Zeilennummer As Long, ZeilenzΣhler As Long, ZeilenlΣnge As Long)
  1290. Dim Anfang As Long
  1291. Dim Achtschritt As Long
  1292. Dim Zeile As Long
  1293. Dim Zeilenanfang As Long
  1294. Dim i As Long
  1295. Dim Bufferstand As Long
  1296. Dim Zeilenstand As Long
  1297. Dim Gr÷▀e As Long
  1298. Dim BytesPerPixel As Long
  1299. Dim Bpp As Long
  1300. Bpp = BitsPerPixel
  1301. If Bpp >= 8 Then
  1302. BytesPerPixel = Bpp / 8
  1303. Else
  1304. BytesPerPixel = 1
  1305. BytesToBits Zeilenbuffer, Me.Bitdepht, ZeilenlΣnge
  1306. End If
  1307. Gr÷▀e = UBound(Zeilenbuffer) + 1
  1308. Zeilenanfang = Me.Width * (Zeilennummer - 1) * BytesPerPixel
  1309. Achtschritt = Me.Width * 8 * BytesPerPixel
  1310. Anfang = (Achtschritt * (ZeilenzΣhler - 1)) + Zeilenanfang
  1311. 'Zeilentyp: 1 = 1; 2 = 5; 3 = 1+5; 4 = 3+7; 5 = 1+3+5+7; 6 = 2+4+6+8; 7 = 1-8;
  1312. Bufferstand = Anfang
  1313. Select Case Zeilentyp
  1314. Case 1
  1315. Do While Zeilenstand < Gr÷▀e
  1316. CopyMemory Buffer(Bufferstand), Zeilenbuffer(Zeilenstand), BytesPerPixel
  1317. Bufferstand = Bufferstand + (8 * BytesPerPixel)
  1318. Zeilenstand = Zeilenstand + BytesPerPixel
  1319. Loop
  1320. Case 2
  1321. Bufferstand = Bufferstand + (4 * BytesPerPixel)
  1322. Do While Zeilenstand < Gr÷▀e
  1323. CopyMemory Buffer(Bufferstand), Zeilenbuffer(Zeilenstand), BytesPerPixel
  1324. Bufferstand = Bufferstand + (8 * BytesPerPixel)
  1325. Zeilenstand = Zeilenstand + BytesPerPixel
  1326. Loop
  1327. Case 3
  1328. Do While Zeilenstand < Gr÷▀e
  1329. CopyMemory Buffer(Bufferstand), Zeilenbuffer(Zeilenstand), BytesPerPixel
  1330. If Zeilenstand + BytesPerPixel < Gr÷▀e Then
  1331. CopyMemory Buffer(Bufferstand + (4 * BytesPerPixel)), Zeilenbuffer(Zeilenstand + BytesPerPixel), BytesPerPixel
  1332. End If
  1333. Bufferstand = Bufferstand + (8 * BytesPerPixel)
  1334. Zeilenstand = Zeilenstand + (2 * BytesPerPixel)
  1335. Loop
  1336. Case 4
  1337. Bufferstand = Bufferstand + (2 * BytesPerPixel)
  1338. Do While Zeilenstand < Gr÷▀e
  1339. CopyMemory Buffer(Bufferstand), Zeilenbuffer(Zeilenstand), BytesPerPixel
  1340. If Zeilenstand + BytesPerPixel < Gr÷▀e Then
  1341. CopyMemory Buffer(Bufferstand + (4 * BytesPerPixel)), Zeilenbuffer(Zeilenstand + BytesPerPixel), BytesPerPixel
  1342. End If
  1343. Bufferstand = Bufferstand + (8 * BytesPerPixel)
  1344. Zeilenstand = Zeilenstand + (2 * BytesPerPixel)
  1345. Loop
  1346. Case 5
  1347. Do While Zeilenstand < Gr÷▀e
  1348. CopyMemory Buffer(Bufferstand), Zeilenbuffer(Zeilenstand), BytesPerPixel
  1349. If Zeilenstand + BytesPerPixel < Gr÷▀e Then
  1350. CopyMemory Buffer(Bufferstand + (2 * BytesPerPixel)), Zeilenbuffer(Zeilenstand + BytesPerPixel), BytesPerPixel
  1351. End If
  1352. If Zeilenstand + (2 * BytesPerPixel) < Gr÷▀e Then
  1353. CopyMemory Buffer(Bufferstand + (4 * BytesPerPixel)), Zeilenbuffer(Zeilenstand + (2 * BytesPerPixel)), BytesPerPixel
  1354. End If
  1355. If Zeilenstand + (3 * BytesPerPixel) < Gr÷▀e Then
  1356. CopyMemory Buffer(Bufferstand + (6 * BytesPerPixel)), Zeilenbuffer(Zeilenstand + (3 * BytesPerPixel)), BytesPerPixel
  1357. End If
  1358. Bufferstand = Bufferstand + (8 * BytesPerPixel)
  1359. Zeilenstand = Zeilenstand + (4 * BytesPerPixel)
  1360. Loop
  1361. Case 6
  1362. Bufferstand = Bufferstand + BytesPerPixel
  1363. Do While Zeilenstand < Gr÷▀e
  1364. CopyMemory Buffer(Bufferstand), Zeilenbuffer(Zeilenstand), BytesPerPixel
  1365. If Zeilenstand + BytesPerPixel < Gr÷▀e Then
  1366. CopyMemory Buffer(Bufferstand + (2 * BytesPerPixel)), Zeilenbuffer(Zeilenstand + BytesPerPixel), BytesPerPixel
  1367. End If
  1368. If Zeilenstand + (2 * BytesPerPixel) < Gr÷▀e Then
  1369. CopyMemory Buffer(Bufferstand + (4 * BytesPerPixel)), Zeilenbuffer(Zeilenstand + (2 * BytesPerPixel)), BytesPerPixel
  1370. End If
  1371. If Zeilenstand + (3 * BytesPerPixel) < Gr÷▀e Then
  1372. CopyMemory Buffer(Bufferstand + (6 * BytesPerPixel)), Zeilenbuffer(Zeilenstand + (3 * BytesPerPixel)), BytesPerPixel
  1373. End If
  1374. Bufferstand = Bufferstand + (8 * BytesPerPixel)
  1375. Zeilenstand = Zeilenstand + (4 * BytesPerPixel)
  1376. Loop
  1377. Case 7
  1378. CopyMemory Buffer(Bufferstand), Zeilenbuffer(0), UBound(Zeilenbuffer) + 1
  1379. End Select
  1380. End Sub
  1381. Private Sub BytesToBits(Bytefeld() As Byte, Bitanzahl As Byte, Gr÷▀e As Long)
  1382. Dim i As Long
  1383. Dim ▄bergabe() As Byte
  1384. Dim Wandeln() As Byte
  1385. Dim EinGr As Long
  1386. Dim z As Long
  1387. EinGr = UBound(Bytefeld) + 1
  1388. Select Case Bitanzahl
  1389. Case 1
  1390. ReDim ▄bergabe((EinGr * 8) - 1)
  1391. For i = 0 To EinGr - 1
  1392. ByteToEinBit Bytefeld(i), Wandeln
  1393. CopyMemory ▄bergabe(z), Wandeln(0), 8
  1394. z = z + 8
  1395. Next i
  1396. Case 2
  1397. ReDim ▄bergabe((EinGr * 4) - 1)
  1398. For i = 0 To EinGr - 1
  1399. ByteToZweiBit Bytefeld(i), Wandeln
  1400. CopyMemory ▄bergabe(z), Wandeln(0), 4
  1401. z = z + 4
  1402. Next i
  1403. Case 4
  1404. ReDim ▄bergabe((EinGr * 2) - 1)
  1405. For i = 0 To EinGr - 1
  1406. ByteToVierBit Bytefeld(i), Wandeln
  1407. CopyMemory ▄bergabe(z), Wandeln(0), 2
  1408. z = z + 2
  1409. Next i
  1410. End Select
  1411. ReDim Preserve ▄bergabe(Gr÷▀e - 1)
  1412. Bytefeld = ▄bergabe
  1413. End Sub
  1414. Private Sub ByteToZweiBit(Number As Byte, Wandeln() As Byte)
  1415. Dim a As Byte
  1416. ReDim Wandeln(3)
  1417. Wandeln(3) = Number And 3
  1418. a = Number And 12
  1419. Wandeln(2) = a / 4
  1420. a = Number And 48
  1421. Wandeln(1) = a / 16
  1422. a = Number And 192
  1423. Wandeln(0) = a / 64
  1424. End Sub
  1425. Private Sub ByteToEinBit(Number As Byte, Wandeln() As Byte)
  1426. Dim a As Byte
  1427. ReDim Wandeln(7)
  1428. Wandeln(7) = Number And 1
  1429. a = Number And 2
  1430. Wandeln(6) = a / 2
  1431. a = Number And 4
  1432. Wandeln(5) = a / 4
  1433. a = Number And 8
  1434. Wandeln(4) = a / 8
  1435. a = Number And 16
  1436. Wandeln(3) = a / 16
  1437. a = Number And 32
  1438. Wandeln(2) = a / 3(6) = a / 2
  1439. a = N
  1440. Wanter Zeilenbuffer hdeln(2) = an4
  1441. WaAB3 W,ber As Br Ap And 3
  1442. a = Number And 12g07) = Nu13 48
  1443. Wandel=aAB3 W,ber A4 = Nu13 48
  1444. W(Left) + CInt(Above) f Le
  1445. WaAB3 W,ber As Br Ap And 3
  1446. a iandeln(2) = +u = el)), BytrByte, Wandeln()eln(2) = +u = e Br Ap And, Wandeln()eln(2) = +u = e Br Ap And, Wandeln()eln(2) = +u = e Br Ap And, Wandeln()eln(2) = +a / 16el)), nd,Ap And, Wandeldelln(3) s Then
  1447. yte) 8
  1448. z = z + 8
  1449. Next inReverseAd 3
  1450. a iandeln( = z + 8
  1451. N2a As Byte
  1452. ReDim W Bytrbi Byte
  1453. ReDim W Bytr1 And 12
  1454. Wanderivate Sub
  1455. N2a e<hen
  1456. yte) 8
  1457. z =nrByte, Wande, es LoEffer ZwissbLong
  1458. Dim Zeiu= 0 Tdr - 1
  1459. ByteToEtesPerPixel)),"Dim Zeiu= 0 T52r1 Andr ZwisAndr Z
  1460. ReDiEnd 
  1461. Case PerPixel)), BytesPerdes = LN
  1462. ReDim t- 1)
  1463. CopyM- 1)
  1464. CopyM- 1)
  1465. Copy 1)
  1466. Copy 1)
  1467. CoponstanCopl = BpType =  Wandeln()eln(2) = anCopl = BpType Wandeln()elaoEtesPerPixelcl = B
  1468. ReDim W Byt4yZeilenstanemory1
  1469. N2at4yZeilenstanem x4yZeilenstanex4yZeilenstane  x4yZeilenstanim W Byt4yZeilenstanemory1
  1470. N2aF W B8\As Gr÷▀e÷▀e÷▀e÷▀e÷▀e÷▀e÷▀e÷▀e W B8\AReverseAd 3
  1471. a ianLBytesgcing
  1472.  / 4
  1473. a =Bub (3 * Byteesgcing
  1474.  /Ese 3
  1475. DoseAd 3elnp1
  1476. N2at4yZeilenstaneen
  1477. yBrstan 1)
  1478. CTI /Ese>r And 32
  1479. Wandeln(np1
  1480. ÷▀e÷▀e W B8\8yZeilensta =Budelln(andeln(n(yZeilen Gr
  1481. z = z ndeln(3) = Pixel)), +u =cPay(16, BudCndestanim
  1482. Copox4yZeilenstanE1)
  1483. CopytOff As sAd 3o
  1484. ÷▀e÷▀(EinGr * 8) - 1)
  1485. Forght8
  1486. If Rest8 > 0 Then
  1487. z = = anCo- =Buxlln(andtefeldoEf4B Thenumber As Byte,▀e÷▀e W B8\8yZeilensta =Bu(
  1488. Re N(x) < Minbits AnsDThe =Budelln(andelPay(16*nction
  1489. Private Sub Init_Decompress(Unmpress(x4yZeilnstRe N(x) < Minbiilenstaneen
  1490. yBrst51)
  1491. CopyM- 1)EinGr * 8) - 1)
  1492. ForgRe N(x) <
  1493. yBrst51)
  1494. C*nBitanCopllenbuffe- 1)
  1495. CopyM- 1)
  1496. Coie Bia(x) <
  1497. ReDim ==
  1498. CopyMie Bia(x) <
  1499. Rs Byte, Zeilennummest8 > 0 Then
  1500. z = = anCo2ToBits(Bytef
  1501.  /Ese 3ntelhen
  1502. z = gRexhen
  1503. oEtesPerPixelcl = B
  1504. ReDim W Byt4yp An
  1505. ReDim t- 1 W By
  1506. End Sub
  1507. Private Sub ByteToZweiBit(Number As Byt 8
  1508. z =nr(ref
  1509.  /Ese 3n,FytesPerPixel
  1510. Forght8o= LN
  1511. ReDim t- 1DmForght8o= LN
  1512. ReDght8o=mber As Byt 8
  1513. z =nr(ref
  1514.  /Ese 3n,FyteAB3 W,beE = BpTy(Dim t- - 1
  1515. ByteTo = Nht8o=mber v4rs Lon:cEtesPerPixelcl = B
  1516. ReDim Wo=mbe Minb8o= LN
  1517. ReDght8o=mber As B(Zeilcoie Bia(x) <
  1518. ReDi As B(r() AsLN
  1519. ReDght8 Tdr - 1
  1520. 3 W,beE = BpTy(Dim t- - 1
  1521. By
  1522. ReDim= gRexhen
  1523. oEt2
  1524. Wandeln(np1
  1525. ÷▀e÷▀e 
  1526. By
  1527. ReDim= Cas
  1528. z = gRexel = Interv==
  1529. CopyMie Bia
  1530. ReDght8o=andeln()el = +u = e Br* Byteesgcing
  1531.  Nht8o=mbgcing
  1532. I2a As Byia
  1533. Ruffer) +ReDght8osgci8 AnzRB = Nht8o=mbgDght8o8o=mbgDght8o8o=mbgDghtrPixel)), ,s Selht8o=mbg5cOt8o=mbgDght8o8o=mbgstand = B5y
  1534. ReDim= CanF+bLonPixel->"el)), +u =cPa Zeilenbuffer(Zeilenstand + Bytes+ (2 * BytesPopyM(i * Byts
  1535. z = gRexel = Interv==AtesPop5AnsDTW The) - 1)
  1536. erv==AtesPoL > 0 Then
  1537. dound(OutSe, RowBytesxel)), 8o=mb + (3Se, ReZPmory ▄bergabe(zyte), RowBytes(0gstand = B=gstadoEf4r As Wen
  1538.  rEeDght8ou= +a / 16Bw
  1539. Endba aCht8o=wZeilenbuffer(Zeilens >  + 7) 
  1540. Filo Men8o=lenbufa B8\8yZeilensta =B), ,sschri8ou= +a / ferstand + (bufa B8\8yZeilensta =Bi(bufa B8\)
  1541. ReDla =Bi(Sub ByteToZweiBit(Number As Byt 8
  1542. z =nr(ref
  1543.  /EanCopl ahC,FytesPffe- 1e 0If Rest8 > 3 .Mie B5ufa B8pTy N2aF3evRox14W Byt4yZeil ByteToZweiBit(NumbeBit(NumbeBit(N"ARWande/ 16Bw
  1544. Endba aCht8o)÷▀e 
  1545. 5 1)
  1546. ge As Long)
  1547. D 3
  1548. Do:==onsta =BTI
  1549. ge As Long)l = +u = e BBandeltandeltandeltandeltandeltaltaseileRox14;gaCht8o=wZeileZndeltander And 32s Wen
  1550.  rEeDghe1c 16B= Number And 16vs Wen
  1551.  rEeDghe1c 16B= Number AndTIo8o=mbgDghtrPixel))Aer AndTIo8oZeileZ= Nhto=mbgDht8o=wZo8oo=mbgDht8o=wZo8oo=mbgDht8o=wfe- 1e 0Iffo=mbgDht8o=wZop8oo=mbgDht8o=wZo8oo=m 1e 0I2BytesPSs Long)1e 0I2)2)1e 0I2) t-m 1e nst- - 16B= Number eileRox14;gaCht8o=nEibgDht8o=wZoe8oo=mbgW=eileRober eileRox1=mbgW5,
  1552. Forght8
  1553. If52MRowByte14;gaCh=nEi> 3eRox1=mbgW5,
  1554. Forg 0I
  1555. By
  1556. R:IaCh=nEs2m3=wZeZeile As L, nst- - 167ndeltandelta>xToZweiBit(Number As Byt 8
  1557. z =nr(ref
  1558.  /EanCopl ahC,Fyp =dci8 AnzRB ▀e The)Fyp W B8\MAeDght8ou= +a / 1,ahC,Fyp =dci8 AnzRB ▀e The)Fyp W B8\MAeDght8ou= +a / 1,ahC,Fyp =dci8 AnzRB ▀e The)Fyp W B
  1559. z =>  + 7) 
  1560. Filo Men8o=lenbufa B8\8yZeilember AndTIo(3 * Byteesgcing
  1561. teestghtI8oo=mbgDhZeio=m 1e 0I2BytesPSs Long)1eTIo(3 * B
  1562. teestghtI8o Zeif/L3 * B
  1563. teeIo(3 * B
  1564. teesteDght8o=mber As Byp =dctghtI8o Zeif/L3 * B
  1565. tTIo(3RB ▀aAnd 16Byte, Pp =dctghtI8opn =dctghtI8ht8wnlΣnge Pp =dctghtI8opn =dctghtI8ht8wnlΣnge Pp =dctghtI8opn =dctghtI8ht8wnlΣn< B8\bgDhZanfang
  1566. 'Zeilentyp:RB ▀e The)Fyp W B8\MB ▀e Theou=l" As Long
  1567. Dites, i- - 16B= Number eileRo(ahC,Fyp =dcClΣn< s Byt 80g5estghtI8oo=mbtrbtrbtnteDght8o=mber A,V
  1568. Endba aCp =dcCh=wZop8*4(o=mberrPixel)),*4(o=mberrPictghtI8opn =dctghtI8ht8u=l" As Long
  1569. Dites, i- - 16B= Number eileRo(ahC,Fyp =dcClΣn< s Byt 80g5estghtl" AeacClΣn<lopn =dctghtengeZeilngeZeilngeZeilngeZeilngeZ6ilng)
  1570. D 3r eileRo(ahC,Fy<
  1571. yBrst51)y 1)
  1572. Copycand)7) 
  1573. Filo Men8o=snBytesPerPix) 
  1574. Filo Men8iRo(ahC,Fy<
  1575. yBr
  1576. ZL = BerechneZhtland)7) 
  1577. Filo MtI8opn) 
  1578. Ficand)7) 
  1579. Filcilterbyte = Buffer(BiytesPeeRoxPmory ▄bergabe(zumber eia=by ▄bergaxncNnsDTWB=gstadPerPbe.CongeZeiN" Anef
  1580.  /Ea = BerechneZhtland)7) +nd)7)▄beteestZeiln+nd)7)tZeiln+nd)lemZeif/obereZhtland)7)eNx) < Minbits Anl" AeacCxncNnsDTW < MinilngeZ6il/EanCopl ahC,F
  1581. yBr
  1582. ZL = y ▄bergaxncNnsDTWB=gstadPerPbe.< s Byt 80l),nlΣn< Mail/EanCopl 1< s r5n< B8\bhandN
  1583. R),nlΣn= Buffer(BiytesPeeRoxPyp =desxel))N3 =desxel))N3 =dc 55srgaxdimber
  1584. oxPyprB ▀aAnd 16Byte, Pb&:RB ▀e The)Fyp W B8\MB ▀e Theou=lxel->"el5gabe(zumbeeff  s r5=mberrPictghtI8)
  1585. Copycand)7) 
  1586. Filo Men8o=seMen8o=seMeilo Men8o=seMen8o=seMeiliberrPictghtI8)opycand)7) 
  1587. Filo MeF▀e Theou=lxel->"el5gabm BufgstadP2+4+6+8; 7 = 1-8)ferPbe.neZhtlan)LN
  1588. R s dctgaxdimber
  1589. oxPyprBytesPer As - 16Ben< Mail/EanCopl 1< s r5n< B8\bhanknst- - e7MeF▀e Theouopl 1< s r5r+ B (8 * BytesPerdst- - e7MeF▀e Theouopl 1< s r5r+ B (8 * BytesPerdst- - e7MeF▀e Theouopl 1< s r5r+ B (8 * BytesPerdst- - e7MeF▀e Theouopl 1< s r5r+ B (8 * BytesPerdst- - e7MeF▀e Theouopl 1< s r5r+ B (8 * BytesPerdst- - e7MeF▀e Theouopl 1< s r5r+ B (8 * BytesPerdst- - e7MeF▀e9= Nut As Byte) As Anl" AeaNE* BytRFPeeRoxPmobgDght8o8ordst- * Me.Height - 1)
  1590. ÷▀e÷n8iRo(uopl 1< s r5r+ B (8 * dst-(8 * dst-(8 * dember And 4
  1591. aest8  r5r+ger, pB As e7MeF▀e ,dst- mber And 4dember And 43i(8 * BytesPerdst- nlΣn<I As Long * By (8 *MgeZr And = BerechneZhtland)7) 
  1592. Filo MtI8opn) 
  1593. Ficand)7) 
  1594. Filcilterbyte = Buffer(BiytesPeeRoxPmory ▄bergabe(zumber eia=by ▄bergaxncNnsDTWB=gstadPerPbe.CongeZeiN" Anef
  1595.  /Ea = BerechneZhtland)7) +nd)7)▄beteestZeiln+nd)7)tZeiln+nd)lemZeif/obereZhtland)7)eNx) < Minbits Annd)lemZeif/obereZhtlaif/obereZh3(8 * dember And 4
  1596. aest8  r5r+ger, pB Ad)lemZeif/oberehtland3
  1597. a iand B8\bgDhNumbNmCand B8\bgnlΣn< Maignd3
  1598. )rrrrrrrrrrrrereZhtlaif/obereZh3(8 * dember Ah
  1599. Ficand)7) 
  1600. Filc,mLgaxncNnsDTWB=gsf/obere,NCI) 
  1601. FiPrivaei4i:d = ) 
  1602. Filc,mLgaxncNnsDTWB)7) 
  1603. FilI= NBytes + RrB8\)
  1604. ReDla =Bi(Sub andbe.Con+nd + RrB8\s + RrB8) 
  1605. st- eaCht Ma + 1=eDla =Bit - 1
  1606. ByteToEtesPerPixel)),"Dim ZeO1terv==
  1607. Cordst- - e7MeF▀e TheouoplSub By Char = CoplSub By ChMeF▀e
  1608. ByteToEtesPerPixel)), CopleouopoByt4cesPerPixeDTWB=gsteF▀e
  1609. ByteTo▀e
  1610. sPerPixeDTWB Theo=e
  1611. ByoEtesPerPixel)), Cop ouopoByt4cesPerPixeDTW44d iSubeLglel)),< s en8o=seMeiliberrPictgh)GgPixeDTW44d iSubeLglel))3 * B
  1612. teestghtDTW4ByteTo▀e
  1613. sPerPixeDTWB T* B
  1614. teestgacNnsDTfer(Bife ,dst- mber And 4h"lenstand + (2)7)r AeteestZei1 (8 *cNnsDTfseMeiMeirehtland3
  1615. a ianlxel->IerPben Cope>r And 32
  1616. Wandp ouopoByt4cesPerPixeDTW44d iSubeLgl0l),nl"y2tNnsDTfsndp ouopoBnd)le5,nl"y2tNns)), Cop ouopoByt4ced 4
  1617. aest8  r5r+ger, pB Ad)lemZeif/oberaPixwnouopoBytsPerdst- nlΣn<I ALglel)tesPerPiS2t4cesPixelerPiuopoByt4YAd)lemZeif/Ei1 (8 *cyeteestZei1 (8 *cNnsDTfseMeiMeirehtlag
  1618. Die
  1619. sPeesPerPiS2t4cesPixeleriS2t4cesPixeleriS2t4cesPsChar = CoplSub By esPixelerIf
  1620. BuffeW44dIf
  1621. BuffeW44dIfeW44dIf
  1622. BuffeW44dIfeW By esPix
  1623. BuffeW44dIfeW44dIf
  1624. BuffeW44dIfere
  1625. sPeer5r+ B (8BixellemZeaPixwnouopoBytsPerdst- nlΣn<I ALglemil/E5r+gerglemil/E5raglemil/E5raglemil/E5eDTWB TheolI